home *** CD-ROM | disk | FTP | other *** search
- ;
- ; TCP/IP support routines
- ;****************************************************************************
- ;* *
- ;* *
- ;* part of NCSA Telnet *
- ;* by Tim Krauskopf, VT100 by Gaige Paulsen, Tek by Aaron Contorer *
- ;* *
- ;* National Center for Supercomputing Applications *
- ;* 152 Computing Applications Building *
- ;* 605 E. Springfield Ave. *
- ;* Champaign, IL 61820 *
- ;* *
- ;****************************************************************************
- ;
- NAME ASMSTUFF
- include model.inc
-
- ifdef Microsoft
- DGROUP group _DATA
- _DATA segment public 'DATA'
- assume DS:DGROUP
- .DATA
- else
- DSEG
- endif
-
- ifdef Microsoft
- _DATA ends
-
- _TEXT segment public 'CODE'
- assume CS:_TEXT
- PUBLIC _IPCHECK, _TCPCHECK, _LONGSWAP, _INTSWAP, _DBG, _N_PUTCHAR
- PUBLIC _SEGSS, _SEGDS, _SEGCS
- PUBLIC _DOS_EXIT
- PUBLIC _N_KBHIT, _N_GETCH
- PUBLIC _N_LMUL
- PUBLIC _N_LDIV
- PUBLIC _N_LMOVE
- PUBLIC _N_MAMOUNT
- PUBLIC _FAR2LONG
- PUBLIC _CANNON
- PUBLIC _LONG2FAR
- else
- ENDDS
- PSEG
- PUBLIC IPCHECK,TCPCHECK,LONGSWAP,INTSWAP,DBG,N_PUTCHAR
- PUBLIC SEGSS, SEGDS, SEGCS
- PUBLIC DOS_EXIT
- PUBLIC N_KBHIT, N_GETCH
- PUBLIC N_LMUL
- PUBLIC N_LDIV
- PUBLIC N_LMOVE
- PUBLIC N_MAMOUNT
- PUBLIC FAR2LONG
- PUBLIC CANNON
- PUBLIC LONG2FAR
- endif
- ;
- ; Routines for general use by the communications programs
- ;
- ;
- ;************************************************************************
- ; DBG
- ; provides a synch point for debugging
- ;
- START_PROC dbg
- nop
- nop
- nop
- ret
- END_PROC dbg
-
- ;
- ;*************************************************************************
- ; Internet header checksum
- ; header checksum is calculated for a higher level program to verify
- ;
- ; USAGE: ipcheck((IPKT *)ptr,(int)len)
- ;
- ; this proc knows that the IP header length is found in the first byte
- ;
- START_PROC IPCHECK
-
- PUSH BP
- MOV BP,SP
- PUSH ES
- PUSH SI
- PUSH DI
-
- MOV SI,[BP+X] ; pointer to data
- MOV CX,[BP+X+2] ; count of words to test
- XOR BX,BX
- CLC
- CHKSUM:
- LODSW ; get next word
- ADC BX,AX ; keep adding
- LOOP CHKSUM ; til' done
- ADC BX,0 ; adds the carry bit in
- ;
- NOT BX ; take one more 1-complement
- MOV AX,BX
-
- POP DI
- POP SI
- POP ES
- POP BP
- RET
-
- END_PROC IPCHECK
- ;
- ; TCP checksum, has two parts, including support for a pseudo-header
- ;
- ; usage: tcpcheck(psptr,tcpptr,tcplen)
- ; char *psptr,*tcpptr; pointers to pseudo header and real header
- ; int tcplen length of tcp packet in checksum
- ;
- START_PROC TCPCHECK
-
- PUSH BP
- MOV BP,SP
- PUSH SI
- PUSH DI
-
- MOV SI,[BP+X] ; pointer to data
- MOV CX,6 ; length of p-hdr in words
- XOR BX,BX ; clear to begin
- CLC
- PCHKSUM:
- LODSW ; get next word
- ADC BX,AX ; keep adding
- LOOP PCHKSUM ; til' done
- ADC BX,0 ; adds the carry bit in
- ;
- ; NOW THE REAL THING
- ;
- MOV SI,[BP+X+2] ; pointer
- MOV CX,[BP+X+4] ; count of bytes to test
- MOV DX,CX ; keep a copy
- SHR CX,1 ; divide by two, round down
- CLC
- RCHKSUM:
- LODSW
- ADC BX,AX ; add to previous running sum
- LOOP RCHKSUM
- ADC BX,0 ; add the last carry in again
- AND DX,1 ; odd # of bytes?
- JZ NOTODD
- LODSB ; get that last byte
- XOR AH,AH ; clear the high portion
- ADD BX,AX ; add the last one in
- ADC BX,0 ; add the carry in, too
- NOTODD:
- NOT BX ; take one more 1-complement
- MOV AX,BX
- POP DI
- POP SI
- POP BP
- RET
-
- END_PROC TCPCHECK
-
- ;
- ;*************************************************************************
- ; longswap
- ; swap the bytes of a long integer from PC
- ; order (reverse) to in-order. This will work both ways.
- ; returns the new long value
- ; usage:
- ; l2 = longswap(l)
- ; long l;
- ;
- ifdef Microsoft
- _LONGSWAP PROC NEAR
- PUSH BP
- MOV BP,SP
-
- MOV AX,[BP+X+2] ; HIGH BYTES OF THE LONG INT
- MOV DX,[BP+X] ; LOW BYTES OF THE LONG INT
- ;
- ; GET THE DATA
- ;
- XCHG AH,AL ; SWAP THEM, THESE ARE NOW LOW
- XCHG DH,DL ; SWAP THE OTHERS
- POP BP
- RET
- _LONGSWAP ENDP
- else
- LONGSWAP PROC NEAR
- PUSH BP
- MOV BP,SP
- MOV BX,[BP+X+2] ; HIGH BYTES OF THE LONG INT
- MOV AX,[BP+X] ; LOW BYTES OF THE LONG INT
- ;
- ; GET THE DATA
- ;
- XCHG AH,AL ; SWAP THEM, THESE ARE NOW LOW
- XCHG BH,BL ; SWAP THE OTHERS
- POP BP
- RET
- LONGSWAP ENDP
- endif
- ;
- ;*************************************************************************
- ; INTSWAP
- ; swap the bytes of an integer, returns the swapped integer
- ;
- ; usage: i = intswap(i);
- ;
- START_PROC INTSWAP
- PUSH BP
- MOV BP,SP
-
- MOV AX,[BP+X]
- XCHG AH,AL
- POP BP
- RET
-
- END_PROC INTSWAP
-
- ;
- ; Support for BIOS calls in NCSA Telnet
- ;
- ; From original code by Tim Krauskopf 1984-1985
- ;
- ; Modified and ported to Lattice C, Sept. 1986
- ; ifdefs for Microsoft C, June 1987
- ; Tim Krauskopf
- ;
- ; Modified for version 2.3 release May 1990 by Heeren Pathak
- ;
- ; National Center for Supercomputing Applications
- ;
-
- ; The subroutines to call from C
- ;
- ;/***************************************************************/
- ; n_putchar(letter)
- ; puts onto screen at current cursOR location
- ;
- START_PROC N_PUTCHAR
-
- PUSH BP
- MOV BP,SP
- PUSH DS
- PUSH ES
- PUSH SI
- PUSH DI
-
-
- MOV AL,[BP+X] ; char to write
-
- MOV BL,3 ; SEND WHATEVER CHAR
- MOV BH,0
- MOV AH,14
- INT 10H
-
- POP DI
- POP SI
- POP ES
- POP DS
- POP BP
- RET
-
- END_PROC N_PUTCHAR
-
- START_PROC SEGSS
- mov ax,ss
- ret
- END_PROC SEGSS
-
- START_PROC SEGCS
- mov ax,cs
- ret
- END_PROC SEGCS
-
- START_PROC SEGDS
- mov ax,ds
- ret
- END_PROC SEGDS
-
-
- START_PROC dos_exit
-
- ; assume dos version 2
-
- PUSH BP
- MOV BP,SP
-
- MOV AL,[BP+X] ; exit code
- mov ah, 4ch
- int 21h
- pop bp ; shouldn't get here
- ret
- END_PROC dos_exit
-
-
- START_PROC n_kbhit
- PUSH BP
- MOV BP,SP
- PUSH DS
- PUSH ES
- PUSH SI
- PUSH DI
-
- MOV AH,1
- INT 16H
- mov ax,0
- jz not_there
- inc ax
-
- not_there:
-
- POP DI
- POP SI
- POP ES
- POP DS
- POP BP
- RET
-
- END_PROC n_kbhit
-
- START_PROC n_getch
- PUSH BP
- MOV BP,SP
- PUSH DS
- PUSH ES
- PUSH SI
- PUSH DI
-
- MOV AH,0
- INT 16H
-
- cmp al,0
- jz special
- xor ah,ah
- special:
- POP DI
- POP SI
- POP ES
- POP DS
- POP BP
- RET
-
- END_PROC n_getch
-
- START_PROC N_LMUL
- PUSH BP
- MOV BP,SP
- PUSH DS
- PUSH ES
- PUSH SI
- PUSH DI
-
- mov ax,[x+bp]
- mov dx,[x+bp+2] ; high
- mov bx,[x+bp+4] ; low
- mov cx,[x+bp+6] ; high
-
- mov bp,dx ; if both high words zero - great
- or bp,cx
- jnz star1
-
- mul bx
- jmp mul_exit
-
- star1:
- mov bp,ax
- push dx
- mul bx
- xchg ax,bp
- xchg cx,dx
- mul dx
- add cx,ax
- pop ax
- mul bx
- add cx,ax
- mov dx,cx ; high
- mov ax,bp ; low
- mul_exit:
- POP DI
- POP SI
- POP ES
- POP DS
- POP BP
- RET
-
- END_PROC N_LMUL
-
- ; expects (long divisor) (long dividend) returns dx:ax
- ISOR_HIGH EQU (X+6)
- ISOR_LOW EQU (X+4)
- DEND_HIGH EQU (X+2)
- DEND_LOW EQU (X)
- ;
- START_PROC N_LDIV
-
- push bp
- mov bp,sp
- push di
- push si
- push bx
- xor di,di
- mov ax,[bp+DEND_HIGH]
- or ax,ax
- jge dvs_1
- inc di
- mov dx,[bp+DEND_LOW]
- neg ax
- neg dx
- sbb ax,0
- mov [bp+DEND_HIGH],ax
- mov [bp+DEND_LOW],dx
- dvs_1: mov ax,[bp+ISOR_HIGH]
- or ax,ax
- jge dvs_2
- inc di
- mov dx,[bp+ISOR_LOW]
- neg ax
- neg dx
- sbb ax,0
- mov [bp+ISOR_HIGH],ax
- mov [bp+ISOR_LOW],dx
- dvs_2: or ax,ax
- jnz dvs_3
- mov cx,[bp+ISOR_LOW]
- mov ax,[bp+DEND_HIGH]
- xor dx,dx
- div cx
- mov bx,ax
- mov ax,[bp+DEND_LOW]
- div cx
- mov dx,bx
- jmp dvs_4
- dvs_3: mov bx,ax
- mov cx,[bp+ISOR_LOW]
- mov dx,[bp+DEND_LOW]
- mov ax,[bp+DEND_HIGH]
- dvs_5: shr bx,1
- rcr cx,1
- shr dx,1
- rcr ax,1
- or bx,bx
- jnz dvs_5
- div cx
- mov si,ax
- mul word ptr [bp+ISOR_HIGH]
- xchg cx,ax
- mov ax,[bp+ISOR_LOW]
- mul si
- add dx,cx
- jb dvs_6
- cmp dx,[bp+DEND_HIGH]
- ja dvs_6
- jb dvs_7
- cmp ax,[bp+DEND_LOW]
- jbe dvs_7
- dvs_6: dec si
- dvs_7: xor dx,dx
- xchg si,ax
- dvs_4: dec di
- jnz dvs_8
- neg dx
- neg ax
- sbb dx,0
- dvs_8: pop bx
- pop si
- pop di
- mov sp,bp
- pop bp
- ret
- END_PROC N_LDIV
-
- START_PROC n_lmove
-
- PUSH BP
- MOV BP,SP
- PUSH DS
- PUSH ES
- PUSH SI
- PUSH DI
-
- mov ax,ds
- mov es,ax ; copy ds
- mov si,[x+bp] ; pointer
- mov cx,[x+bp+2] ; no of words to move
- mov ax,8700h ; extended memory block move
- int 15h
- jc n_l_err
- xor ax,ax
- jmp n_l_out
- n_l_err:
- mov al,ah
- xor ah,ah
- n_l_out:
- POP DI
- POP SI
- POP ES
- POP DS
- POP BP
- RET
-
- END_PROC n_lmove
-
-
- START_PROC n_mamount
-
- PUSH BP
- MOV BP,SP
- PUSH DS
- PUSH ES
- PUSH SI
- PUSH DI
- mov ax,8800h ; extended memory amount
- int 15h
-
- POP DI
- POP SI
- POP ES
- POP DS
- POP BP
- RET
-
- END_PROC n_mamount
-
- START_PROC far2long
- PUSH BP
- MOV BP,SP
- mov dx,[x+2+bp] ; high
- xor ax,ax ; clear low for now
- mov cx,12
- f2lp:
- shr dx,1 ; shift low bit into carry
- rcr ax,1 ; carry into top bit
- loop f2lp
-
- add ax,[x+bp] ; low
- adc dx,0
-
- POP BP
- RET
-
- END_PROC far2long
-
- START_PROC cannon
- PUSH BP
- MOV BP,SP
- mov dx,[x+2+bp] ; high
- mov ax,[x+bp] ; low
- mov cl,4
- shr ax, cl
- add dx,ax ; this could overflow
- ; --- but not unless fxxxx + ffff
- mov ax,[x+bp] ; low
- and ax,0fh
- POP BP
- RET
-
- END_PROC cannon
-
- START_PROC long2far
- PUSH BP
- MOV BP,SP
- mov dx,[x+2+bp] ; high
- mov cl,4
- shr dx,1 ; put into carry
- rcr dx,cl ; low 4 bits into high four bits
- and dx,0f000h
- mov ax,[x+bp] ; low
- mov cl,4
- shr ax,cl ; divide by 16
- add dx,ax ; could or
- mov ax,[x+bp] ; low again
- and ax,0fh
- POP BP
- RET
-
- END_PROC long2far
-
- ifdef Microsoft
- _TEXT ends
-
- else
- ENDPS
- endif
- END
-
-
-